home *** CD-ROM | disk | FTP | other *** search
- ;********************************************************
- ;* *
- ;* N W D r v *
- ;* *
- ;* Function : NetWare driver for processing "SEND", *
- ;* and "RECEIVE" operation. *
- ;* This function is interrupt handler *
- ;* with number 6eh. *
- ;* Input: In AH contains function code. *
- ;* Function code may be: *
- ;* TEST - test if int 6f handler is *
- ;* active; *
- ;* OPEN - open the socket for I/O *
- ;* operation, and activate *
- ;* interface functions. In DS:DX's *
- ;* address of Input_Control_Record *
- ;* (see drvicr.inc for detailes); *
- ;* CLOSE - close the socket; *
- ;* SEND - send block, *
- ;* DS:DX points the block for *
- ;* transmittion; *
- ;* DEACT - deactivisation of driver (reset *
- ;* old INT 6fh handler and free *
- ;* allocated memory. *
- ;* DS:DX points appropriate memory block. *
- ;* Output: Condition code in AX. *
- ;* Last modification: 92-12-01 17:08. *
- ;* *
- ;* CopyRight 1995. Nicholas Poljakov all rights reserved.*
- ;* *
- ;********************************************************
- .MODEL TINY
- .DOSSEG
-
- include c:\lu62\novell\inc\ipxhdr.inc
- include c:\lu62\novell\inc\seg.inc
- include c:\lu62\novell\inc\drvicr.inc
- include c:\m61\include\macros.inc
-
- EXTRN DrvSend : PROC
- EXTRN OffInt6f: WORD
- EXTRN SegInt6f: WORD
- EXTRN MyPSP : WORD
-
- PUBLIC int6f, Rcv_Exit, Rcv_off, ipxProc, CheckAddr, ipxECB, CancelECB
- PUBLIC Rcv_seg, Codes, ExTable, bufArea, PStart, DrvOpen, OpExit
- PUBLIC DrvClose, Deact, Dummy, RcvESR, RcvContin, PrepECB, DrvTest
- PUBLIC ActLU, ActLuMsg, LocalS, StAddrCycl, CallDrvSend
-
-
- OPEN EQU 00h
- SEND EQU 01h
- CLOSE EQU 02h
- DEACT EQU 03h
- CHKADDR EQU 04h
- TESTEX EQU 33h
-
-
- .CODE
- int6f PROC FAR
-
- jmp PStart
-
- ipxProc DD 0 ; IPX entry point
- Rcv_Exit DD 0
- ORG Rcv_Exit
- Rcv_off DW ?
- Rcv_seg DW ?
-
- Codes DB OPEN,CLOSE,SEND,DEACT,CHKADDR,TESTEX,255
- Count EQU $ - Codes
- ExTable DW DrvOpen
- DW DrvClose
- DW DrvSend
- DW Deact
- DW CheckAddr
- DW DrvTest
- DW Dummy
-
- ipxECB IPXECB <>
- ipxHDR IPXHDR <>
- ipxAddr INTADDR <> ; IPX internetwork address
- ImmAddr DB 6 DUP(?) ; Immediate Address of node.
- bufArea DB 546 dup(0)
-
- LocalS DB 0 ; "Local_Send" indicator
- MsgFrom DB 0 ; First byte of Node Address
- ActLuMsg SEGPRF <, 9, 0>
- RQB DB 16 dup(0) ; reserved RQD field
- MsgTag DB 1
- NameLu DB 0,0,0,0,0,0,0,0 ; Activate LU message
-
- PStart:
- @SaveRegs ax,bx,cx,ds,dx,si,di,es,bp
- mov bp, sp
-
- sti
- mov cx, cs
- mov ds, cx
- mov cx, Count
- mov di, OFFSET Codes
- push cs
- pop es
- mov al, ah
- cld
- repne scasb
- sub di,(OFFSET Codes)+1 ; Point to key
- shl di,1 ; Adjust pointer for word addresses
- call ExTable[di] ; Call procedure
- jc IntExit ; return code was already set.
- mov WORD PTR [bp + 16], ax ; set RETURN CODE in AX
-
- IntExit:
- @RestoreRegs
- iret
-
- int6f ENDP
-
- DrvOpen PROC
- ;***************************************************
- ;* First, fetch address of IPX entry point *
- ;***************************************************
-
- mov ax, 7a00h
- int 2fh
- cmp al, 0ffh
- je IPXexist
- mov ax, 0ffffh
- jmp OpExit ; in ax - bad return code
- IPXexist:
- mov ax, es
- mov WORD PTR ipxProc, di
- mov WORD PTR ipxProc + 2, ax
-
- ; Set Rcv_Exit value
-
- les bx, DWORD PTR [bp + 8] ; input DX value
- mov ax, WORD PTR es:[bx].RcvSbr
- mov Rcv_off, ax
- mov ax, WORD PTR es:[bx].RcvSbr + 2
- mov Rcv_seg, ax
-
- ;***************************************************
- ; Second, Open the socket... *
- ;***************************************************
-
- xor bx, bx ; open socket function
- mov ax, 0ffffh ; open until closed
- mov dx, MY_SOCKET
- call ipxProc
- and ax, ax ; is it O.K! ?
- jnz OpExit ; no... exit.
-
- ;***************************************************
- ;* Then send "Activate_LU" broadcasting message *
- ;* and set "listening" request *
- ;***************************************************
-
- call ActLU
- call PrepECB
-
- ; And exit...
-
- OpExit:
- clc
- ret
- DrvOpen ENDP
-
- DrvClose PROC
-
- ; Close my socket
-
- mov bx, 1
- mov dx, MY_SOCKET
- call ipxProc
-
- clc
- ret
- DrvClose ENDP
-
- ;***************************************************
- ;* *
- ;* Deactivation LU procedure. *
- ;* *
- ;* Function : 1). Sends broadcasting message *
- ;* "Deactivate_LU". *
- ;* 2). Close socket. *
- ;* 3). Restore pointer to old INT 6fh *
- ;* handler. *
- ;* 4) And free the memory allocated for*
- ;* this program. *
- ;* *
- ;***************************************************
- Deact PROC
- ;*
- ;* Send broadcasting "Deactivisation_LU" message
- ;*
- mov ipxHDR.PType, 0 ; control packet
- mov MsgTag, 2
- call ActLU
-
- ;* Close my socket
-
- mov bx, 1
- mov dx, MY_SOCKET
- call ipxProc
- ;*
- ;* Restory Old Int6fh vector
- ;*
- cli
- mov ax, 10h
- mov es, ax
- mov ax, OffInt6f
- mov WORD PTR es:[0bch], ax ; Old INT6f, offset
- mov ax, SegInt6f
- mov WORD PTR es:[0beh], ax ; Old INT6f, segment
- sti
-
- ;*
- ;* And free program segment...
- ;*
- mov ax, MyPSP
- mov es, ax
- mov ax, 4900h
- int 21h ; Free code segment
-
- clc
- ret
- Deact ENDP
-
- Dummy PROC
- clc
- ret
- Dummy ENDP
-
- CheckAddr PROC
- ;***************************************************
- ;* *
- ;* Check Node address before send block to it. *
- ;* *
- ;***************************************************
-
- les bx, DWORD PTR [bp + 8] ; input DS:DX values
-
- ; Prepare Address buffer
-
- mov ax, WORD PTR es:[bx]
- mov WORD PTR ipxAddr.NodeAddr, ax
- mov ax, WORD PTR es:[bx + 2]
- mov WORD PTR ipxAddr.NodeAddr + 2, ax
- mov ax, WORD PTR es:[bx + 4]
- mov WORD PTR ipxAddr.NodeAddr + 4, ax
- mov si, OFFSET ipxAddr
- mov di, OFFSET ImmAddr
- mov bx, cs
- mov es, bx
- mov bx, 2
- call ipxProc ; get local target for input node address
- xor ah, ah
- and ax, ax ; check return code from IPX
- jnz ChkExit ; bad return code... exit.
-
- mov di, WORD PTR [bp + 8] ; input DX value
- mov ax, WORD PTR [bp + 12] ; input DS value
- mov es, ax
- mov si, OFFSET ImmAddr
- mov cx, cs
- mov ds, cx
- mov cx, 6
- cld
- rep movsb ; copy returned address to field
- ; that pointes by input DS:DX
- xor ax, ax ; O.K! return code
-
- ChkExit:
- clc
- ret
- CheckAddr ENDP
-
-
- ;***************************************************
- ;* *
- ;* ESR for receiving incoming packet. *
- ;* ES:SI points to appropriate ECB. *
- ;* AX - source indicator *
- ;* *
- ;***************************************************
- RcvESR PROC FAR
- cli
- mov cx, cs
- mov ds, cx
-
- cmp ipxECB.RetCode,0 ; is it normal receive ?
- jne RcvContin
- les di, ipxECB.SAddr ; address of data block
- mov cl, BYTE PTR es:[di] ; first byte of Network Address
- mov MsgFrom, cl ; Save first byte of Node address
- lea si, ipxECB.PAddr ; pointer to partner address field
- mov cx, 6
- cld
- rep movsb ; mov p. addr. in SEGPRF.PAddr
- les si, ipxECB.FAddr ; ES:SI pointes to IPX header
- mov cx, es:[si].PLt ; total length of received data block
- xchg ch, cl
- sub cx, 30 ; length of data block
- mov dx, WORD PTR ipxECB.SAddr
- mov ax, WORD PTR ipxECB.SAddr + 2
- xor bh, bh
- mov bl, ipxHDR.PType ; packet type
- push ds
- mov ds, ax ; DS:DX now points to input buffer
- mov ax, bx ; message type indicator
- pushf ; Call "_interrupt" function for read block
- call Rcv_Exit
- pop ds
- and bx, bx ; is it a control message ?
- jnz RcvContin ; no...
- les bx, ipxECB.SAddr ; ES:BX points to message field
- cmp BYTE PTR es:[bx + PRFLT], 2 ; is it "Deactivate_LU" message ?
- je RcvContin
- cmp MsgFrom, 0ffh ; is it broadcasting message ?
- jne RcvContin
- mov si, bx
- mov di, OFFSET ActLuMsg
- mov cx, 6
- cld
- rep movsb ; set address of source of message
- call ActLU ; send response to "Activate_Lu"
- ; message
-
- RcvContin:
- call PrepECB
-
- ret
- RcvESR ENDP
-
- PrepECB PROC
-
- ; Prepare ECB for receivig packets
-
- cmp ipxECB.InUse, 0feh ; is ECB in listening mode?
- je PrepExit
- mov ax, OFFSET RcvESR
- mov WORD PTR ipxECB.ESR, ax ; set ESR address
- mov ax, cs ; for
- mov WORD PTR ipxECB.ESR + 2, ax ; block receiving
- mov ipxECB.SocNum, MY_SOCKET
- mov bx, OFFSET ipxHDR
- mov WORD PTR ipxECB.FAddr, bx ; set ipx header address
- mov WORD PTR ipxECB.FAddr + 2, ax
- mov ipxECB.FLt, 30 ; length of ipx header
- mov bx, OFFSET bufArea
- mov WORD PTR ipxECB.SAddr, bx ; set address of data block
- mov WORD PTR ipxECB.SAddr + 2, ax
- mov ipxECB.SLt, 546 ; length of data block
- mov ipxECB.FragNum, 2 ; two fragments
-
- mov bx, cs
- mov es, bx
- mov bx, 4
- mov si, offset ipxECB
- call ipxProc
-
- PrepExit:
- ret
- PrepECB ENDP
-
- DrvTest PROC
- mov WORD PTR [bp + 16], 5555h ; set output AX value
- ; 5555h - indicates that
- ; int 6fh is exist.
- xor ax, ax ; local return code
- stc ; to prevent reset
- ; global return code
- ret
- DrvTest ENDP
-
- CancelECB PROC
- @SaveRegs ax,bx,cx,si,es
- CnPrep:
- mov si, cs
- mov es, si
- mov si, OFFSET ipxECB
- mov bx, 6 ; cancel request
- call ipxProc
- and al, al
- jz CnExit
- cmp al, 0ffh
- je CnExit
- cmp al, 0ffh
- jne CnExit
-
- mov cx, 0ffffh
- sti
- WaitCycl:
- loop WaitCycl ; wait for end of transmittion
- jmp short CnPrep
-
- CnExit:
- @RestoreRegs
- ret
- CancelECB ENDP
-
- ;***************************************************
- ;* *
- ;* Activate LU procedure. *
- ;* Function: Send broadcasting "Activate_LU" *
- ;* message. *
- ;* *
- ;***************************************************
-
- ActLU PROC
-
- ; Set address of broadcasting message.
-
- cmp ipxHDR.PType, 0 ; is it response to control message?
- je CallDrvSend ; yes, skip address and name setting
-
- mov bx, OFFSET ActLuMsg
- mov cx, 6
- StAddrCycl:
- mov BYTE PTR cs:[bx], 0ffh
- inc bx
- loop StAddrCycl
-
- ; Set Lu_Name field in "Activate_LU" message.
-
- lds si, DWORD PTR [bp + 8] ; input DS:DX values
- lea si, ds:[si].LuName
- mov di, cs
- mov es, di
- mov di, OFFSET NameLu
- mov cx, 8
- cld
- rep movsb ; move LU name begins to RH + 1 location
- mov ax, cs
- mov ds, ax
-
- ; Call "DrvSend function".
-
- CallDrvSend:
- mov LocalS, 1 ; ON a "local_send" operation
- call DrvSend
- mov LocalS, 0 ; OFF a "local_send" operation
-
- ret
- ActLU ENDP
-
- END
-